home *** CD-ROM | disk | FTP | other *** search
- ;;; CMPTOP Compiler top-level.
- ;;;
- ;; (c) Copyright Taiichi Yuasa and Masami Hagiya, 1984. All rights reserved.
- ;; Copying of this file is authorized to users who have executed the true and
- ;; proper "License Agreement for Kyoto Common LISP" with SIGLISP.
-
- (in-package 'compiler)
-
- (defvar *objects* nil)
- (defvar *constants* nil)
- (defvar *sharp-commas* nil)
-
- ;;; *objects* holds ( { object vv-index }* ).
- ;;; *constants* holds ( { symbol vv-index }* ).
- ;;; *sharp-commas* holds ( vv-index* ), indicating that the value
- ;;; of each vv should be turned into an object from a string before
- ;;; defining the current function during loading process, so that
- ;;; sharp-comma-macros may be evaluated correctly.
-
- (defvar *global-funs* nil)
-
- ;;; *global-funs* holds
- ;;; ( { global-fun-name cfun }* )
-
- (defvar *closures* nil)
- (defvar *local-funs* nil)
-
- ;;; *closure* holds fun-objects for closures.
-
- (defvar *compile-time-too* nil)
- (defvar *eval-when-compile* t)
- (defvar *top-level-forms* nil)
- (defvar *non-package-operation* nil)
-
- ;;; *top-level-forms* holds ( { top-level-form }* ).
- ;;;
- ;;; top-level-form:
- ;;; ( 'DEFUN' fun-name cfun lambda-expr doc-vv sp)
- ;;; | ( 'DEFMACRO' macro-name cfun lambda-expr doc-vv sp)
- ;;; | ( 'ORDINARY' cfun expr)
- ;;; | ( 'DECLARE' var-name-vv )
- ;;; | ( 'DEFVAR' var-name-vv expr doc-vv)
- ;;; | ( 'CLINES' string )
- ;;; | ( 'DEFCFUN' header vs-size body)
- ;;; | ( 'DEFENTRY' fun-name cfun cvspecs type cfun-name )
- ;;; | ( 'SHARP-COMMA' vv )
-
- (defvar *reservations* nil)
- (defvar *reservation-cmacro* nil)
-
- ;;; *reservations* holds (... ( cmacro . value ) ...).
- ;;; *reservation-cmacro* holds the cmacro current used as vs reservation.
-
- (defvar *global-entries* nil)
-
- ;;; *global-entries* holds (... ( fname cfun return-types arg-type ) ...).
-
- ;;; Package operations.
-
- (si:putprop 'make-package t 'package-operation)
- (si:putprop 'in-package t 'package-operation)
- (si:putprop 'shadow t 'package-operation)
- (si:putprop 'shadowing-import t 'package-operation)
- (si:putprop 'export t 'package-operation)
- (si:putprop 'unexport t 'package-operation)
- (si:putprop 'use-package t 'package-operation)
- (si:putprop 'unuse-package t 'package-operation)
- (si:putprop 'import t 'package-operation)
- (si:putprop 'provide t 'package-operation)
- (si:putprop 'require t 'package-operation)
-
- ;;; Pass 1 top-levels.
-
- (si:putprop 'eval-when 't1eval-when 't1)
- (si:putprop 'progn 't1progn 't1)
- (si:putprop 'defun 't1defun 't1)
- (si:putprop 'defmacro 't1defmacro 't1)
- (si:putprop 'clines 't1clines 't1)
- (si:putprop 'defcfun 't1defcfun 't1)
- (si:putprop 'defentry 't1defentry 't1)
- (si:putprop 'defla 't1defla 't1)
- (si:putprop 'defvar 't1defvar 't1)
-
- ;;; Top-level macros.
-
- (si:putprop 'defconstant t 'top-level-macro)
- (si:putprop 'defparameter t 'top-level-macro)
- (si:putprop 'defstruct t 'top-level-macro)
- (si:putprop 'deftype t 'top-level-macro)
- (si:putprop 'defsetf t 'top-level-macro)
-
- ;;; Pass 2 initializers.
-
- (si:putprop 'defun 't2defun 't2)
- (si:putprop 'defmacro 't2defmacro 't2)
- (si:putprop 'ordinary 't2ordinary 't2)
- (si:putprop 'declare 't2declare 't2)
- (si:putprop 'sharp-comma 't2sharp-comma 't2)
- (si:putprop 'defentry 't2defentry 't2)
- (si:putprop 'defvar 't2defvar 't2)
-
- ;;; Pass 2 C function generators.
-
- (si:putprop 'defun 't3defun 't3)
- (si:putprop 'defmacro 't3defmacro 't3)
- (si:putprop 'clines 't3clines 't3)
- (si:putprop 'defcfun 't3defcfun 't3)
- (si:putprop 'defentry 't3defentry 't3)
-
-
- (defun t1expr (form &aux (*current-form* form) (*first-error* t))
- (catch *cmperr-tag*
- (when (consp form)
- (let ((fun (car form)) (args (cdr form)) fd)
- (declare (object fun args))
- (cond
- ((symbolp fun)
- (cond ((eq fun 'si:|#,|)
- (cmperr "Sharp-comma-macro is in a bad place."))
- ((get fun 'package-operation)
- (when *non-package-operation*
- (cmpwarn "The package operation ~s was in a bad place."
- form))
- (when *compile-time-too* (cmp-eval form))
- (wt-data-package-operation form))
- ((setq fd (get fun 't1))
- (when *compile-print* (print-current-form))
- (funcall fd args))
- ((get fun 'top-level-macro)
- (when *compile-print* (print-current-form))
- (t1expr (cmp-macroexpand-1 form)))
- ((get fun 'c1) (t1ordinary form))
- ((setq fd (macro-function fun))
- (t1expr (cmp-expand-macro fd fun (cdr form))))
- (t (t1ordinary form))
- ))
- ((consp fun) (t1ordinary form))
- (t (cmperr "~s is illegal function." fun)))
- )))
- )
-
- (defun ctop-write (name &aux (vv-reservation (next-cmacro)) def)
-
- (setq *top-level-forms* (reverse *top-level-forms*))
-
- ;;; Initialization function.
- (let ((*vs* 0) (*max-vs* 0) (*clink* nil) (*ccb-vs* 0) (*level* 0)
- (*reservation-cmacro* (next-cmacro)))
- (wt-nl1
- "init_" name "(start,size,data)char *start;int size;object data;")
- (wt-nl1 "{ register object *base=vs_top;"
- "register object *sup=base+VM" *reservation-cmacro*
- ";vs_top=sup;vs_check;")
- (wt-nl "Cstart=start;Csize=size;Cdata=data;set_VV(VV,VM"
- vv-reservation ",data);")
-
- (dolist* (form *top-level-forms*)
- (when (setq def (get (car form) 't2))
- (apply def (cdr form))))
- (wt-nl "vs_top=vs_base=base;")
- (wt-nl1 "}")
- (push (cons *reservation-cmacro* *max-vs*) *reservations*)
- )
-
- ;;; C function definitions.
- (dolist* (form *top-level-forms*)
- (when (setq def (get (car form) 't3))
- (apply def (cdr form))))
-
- ;;; Local function and closure function definitions.
- (let (lf)
- (block local-fun-process
- (loop
- (when (endp *local-funs*) (return-from local-fun-process))
- (setq lf (car *local-funs*))
- (pop *local-funs*)
- (apply 't3local-fun lf))))
-
- ;;; Global entries for directly called functions.
-
- (dolist* (x *global-entries*)
- (apply 'wt-global-entry x))
-
- ;;; Declarations in h-file.
- (wt-h "static char *Cstart;static int Csize;static object Cdata;")
- (dolist* (fun *closures*) (wt-h "static LC" (fun-cfun fun) "();"))
- (dolist* (x *reservations*)
- (wt-h "#define VM" (car x) " " (cdr x)))
- (incf *next-vv*)
- (wt-h "#define VM" vv-reservation " " *next-vv*)
- (if (zerop *next-vv*)
- (wt-h "static object VV[1];")
- (wt-h "static object VV[" *next-vv* "];"))
- )
-
- (defun t1eval-when (args &aux (load-flag nil) (compile-flag nil)
- (eval-flag nil))
- (declare (object load-flag compile-flag eval-flag))
- (when (endp args) (too-few-args 'eval-when 1 0))
- (dolist** (situation (car args))
- (case situation
- (load (setq load-flag t))
- (compile (setq compile-flag t))
- (eval (setq eval-flag t))
- (otherwise (cmperr "The EVAL-WHEN situation ~s is illegal."
- situation))))
- (cond (load-flag
- (let ((*compile-time-too*
- (or compile-flag (and *compile-time-too* eval-flag))))
- (dolist** (form (cdr args)) (t1expr form))))
- ((or compile-flag (and *compile-time-too* eval-flag))
- (setq *non-package-operation* t)
- (dolist** (form (cdr args)) (cmp-eval form))))
- )
-
- (defun t1progn (args) (dolist** (form args) (t1expr form)))
-
- (defun t1defun (args)
- (when (or (endp args) (endp (cdr args)))
- (too-few-args 'defun 2 (length args)))
- (cmpck (not (symbolp (car args)))
- "The function name ~s is not a symbol." (car args))
- (when *compile-time-too* (cmp-eval (cons 'defun args)))
- (setq *non-package-operation* t)
- (let ((*vars* nil) (*funs* nil) (*blocks* nil) (*tags* nil) lambda-expr
- (*sharp-commas* nil) (*special-binding* nil)
- (cfun (or (get (car args) 'Ufun) (next-cfun)))
- (doc nil) (fname (car args)))
- (declare (object fname))
- (setq lambda-expr (c1lambda-expr (cdr args) fname))
- (when (cadddr lambda-expr)
- (setq doc (add-object (cadddr lambda-expr))))
- (add-load-time-sharp-comma)
- (push (list 'defun fname cfun lambda-expr doc *special-binding*)
- *top-level-forms*)
- (push (cons fname cfun) *global-funs*)
-
- (when
- (and
- (get fname 'proclaimed-function)
- (let ((lambda-list (caddr lambda-expr)))
- (declare (object lambda-list))
- (and (null (cadr lambda-list)) ;;; no optional
- (null (caddr lambda-list)) ;;; no rest
- (null (cadddr lambda-list)) ;;; no keyword
- (< (length (car lambda-list)) 10)
- ;;; less than 10 requireds
- ;;; For all required parameters...
- (do ((vars (car lambda-list) (cdr vars))
- (types (get fname 'proclaimed-arg-types) (cdr types)))
- ((endp vars)
- (endp types))
- (declare (object vars types))
- (let ((var (car vars)))
- (declare (object var))
- (unless
- (and (eq (var-kind var) 'LEXICAL)
- (not (var-ref-ccb var))
- (not (eq (var-loc var) 'clb))
- (type-and (car types) (var-type var))
- (or (member (car types)
- '(fixnum character
- long-float short-float))
- (eq (var-loc var) 'object)
- (not (member var
- (info-changed-vars
- (cadr lambda-expr)))))
- )
- (return nil))))))
- (numberp cfun))
- (push (list fname
- (get fname 'proclaimed-arg-types)
- (get fname 'proclaimed-return-type)
- t
- (not (member (get fname 'proclaimed-return-type)
- '(fixnum character long-float short-float)))
- (make-inline-string
- cfun (get fname 'proclaimed-arg-types)))
- *inline-functions*))
- )
- )
-
- (defun make-inline-string (cfun args)
- (if (null args)
- (format nil "LI~d()" cfun)
- (let ((o (make-array 100 :element-type 'string-char :fill-pointer 0)))
- (format o "LI~d(" cfun)
- (do ((l args (cdr l))
- (n 0 (1+ n)))
- ((endp (cdr l))
- (format o "#~d)" n))
- (declare (fixnum n))
- (format o "#~d," n))
- o)))
-
- (defun t2defun (fname cfun lambda-expr doc sp &aux (vv (add-symbol fname)))
- (declare (ignore lambda-expr sp))
- (when doc
- (wt-nl "(void)putprop(VV[" vv "],VV[" doc "],siSfunction_documentation);")
- (wt-nl) (reset-top)
- )
- (cond ((numberp cfun)
- (wt-h "static L" cfun "();")
- (wt-nl "MF(VV[" vv "],L" cfun ",start,size,data);"))
- (t (wt-h cfun "();")
- (wt-nl "MF(VV[" vv "]," cfun ",start,size,data);")))
- )
-
- (defun t3defun (fname cfun lambda-expr doc sp &aux inline-info requireds)
- (declare (ignore doc) (object requireds))
- (cond
- ((setq inline-info (assoc fname *inline-functions*))
- (setq requireds (caaddr lambda-expr))
-
- ;;; Add global entry information.
- (push (list fname cfun (cadr inline-info) (caddr inline-info))
- *global-entries*)
-
- ;;; Local entry
- (let* ((*vs* 0) (*max-vs* 0) (*level* 0) (*ccb-vs* 0) (*clink* nil)
- (*exit* (case (caddr inline-info)
- (fixnum 'return-fixnum)
- (character 'return-character)
- (long-float 'return-long-float)
- (short-float 'return-short-float)
- (otherwise 'return-object)))
- (*unwind-exit* (list *exit*))
- (*value-to-go* *exit*)
- (*reservation-cmacro* (next-cmacro))
- (*sup-used* nil)
- (*base-used* nil))
-
- (do ((vl requireds (cdr vl))
- (types (cadr inline-info) (cdr types)))
- ((endp vl))
- (declare (object vl types))
- (setf (var-kind (car vl))
- (case (car types)
- (fixnum 'FIXNUM)
- (character 'CHARACTER)
- (long-float 'LONG-FLOAT)
- (short-float 'SHORT-FLOAT)
- (otherwise 'OBJECT))
- )
- (setf (var-loc (car vl)) (next-cvar)))
- (wt-comment "local entry for function " fname)
- (wt-h "static " (rep-type (caddr inline-info)) "LI" cfun "();")
- (wt-nl1 "static " (rep-type (caddr inline-info)) "LI" cfun "(")
- (do ((vl requireds (cdr vl)))
- ((endp vl))
- (declare (object vl))
- (let ((cvar (next-cvar)))
- (setf (var-loc (car vl)) cvar)
- (wt "V" cvar))
- (unless (endp (cdr vl)) (wt ",")))
- (wt ")")
- (when requireds
- (wt-nl1)
- (do ((vl requireds (cdr vl))
- (types (cadr inline-info) (cdr types))
- (prev-type nil))
- ((endp vl) (wt ";"))
- (declare (object vl))
- (if prev-type
- (if (eq (car types) prev-type)
- (wt ",")
- (wt ";" (rep-type (car types))))
- (wt (rep-type (car types))))
- (setq prev-type (car types))
- (wt "V" (var-loc (car vl)))))
-
- ;;; Now the body.
- (let ((cm *reservation-cmacro*)
- (*tail-recursion-info*
- (if *do-tail-recursion* (cons fname requireds) nil))
- (*unwind-exit* *unwind-exit*))
- (wt-nl1 "{ VMB" cm " VMS" cm " VMV" cm)
- (when sp (wt-nl "bds_check;"))
- (when *compiler-push-events* (wt-nl "ihs_check;"))
- (when *tail-recursion-info*
- (push 'tail-recursion-mark *unwind-exit*)
- (wt-nl1 "TTL:;"))
- (c2expr (caddr (cddr lambda-expr)))
- (wt-nl1 "}")
- (push (cons cm *max-vs*) *reservations*)
- (if (and (zerop *max-vs*) (not *base-used*))
- (wt-h "#define VMB" cm)
- (wt-h "#define VMB" cm " register object *base=vs_top;"))
- (if *sup-used*
- (wt-h "#define VMS" cm
- " register object *sup=vs_top+" *max-vs*
- ";vs_top=sup;")
- (if (zerop *max-vs*)
- (wt-h "#define VMS" cm)
- (wt-h "#define VMS" cm " vs_top += " *max-vs* ";")))
- (if (zerop *max-vs*)
- (wt-h "#define VMV" cm)
- (if *safe-compile*
- (wt-h "#define VMV" cm " vs_reserve(" *max-vs* ");")
- (wt-h "#define VMV" cm " vs_check;")))
- (if (zerop *max-vs*)
- (wt-h "#define VMR" cm "(VMT" cm ") return(VMT" cm ");")
- (if (member (caddr inline-info)
- '(fixnum character long-float short-float))
- (let ((cvar (next-cvar)))
- (wt-h "#define VMR" cm "(VMT" cm ")"
- " {" (rep-type (caddr inline-info)) "V" cvar
- "=VMT" cm ";vs_top=base;return(V" cvar ");}"))
- (wt-h "#define VMR" cm "(VMT" cm ")"
- " {CMPtemp=VMT" cm ";vs_top=base;return(CMPtemp);}")))
- )
- ))
- (t
- (let ((*vs* 0) (*max-vs* 0) (*level* 0) (*ccb-vs* 0) (*clink* nil)
- (*exit* 'return) (*unwind-exit* '(return))
- (*value-to-go* 'return) (*reservation-cmacro* (next-cmacro)))
-
- (wt-comment "function definition for " fname)
- (if (numberp cfun)
- (wt-nl1 "static L" cfun "()")
- (wt-nl1 cfun "()"))
- (wt-nl1 "{ register object *base=vs_base;")
- (wt-nl "register object *sup=base+VM" *reservation-cmacro* ";")
- (if *safe-compile*
- (wt-nl "vs_reserve(VM" *reservation-cmacro* ");")
- (wt-nl "vs_check;"))
- (when sp (wt-nl "bds_check;"))
- (when *compiler-push-events* (wt-nl "ihs_check;"))
- (c2lambda-expr (caddr lambda-expr) (caddr (cddr lambda-expr)) fname)
- (wt-nl1 "}")
- (push (cons *reservation-cmacro* *max-vs*) *reservations*)
- )))
- )
-
- (defun wt-global-entry (fname cfun arg-types return-type)
- (wt-comment "global entry for the function " fname)
- (wt-nl1 "static L" cfun "()")
- (wt-nl1 "{ register object *base=vs_base;")
- (when (or *safe-compile* *compiler-check-args*)
- (wt-nl "check_arg(" (length arg-types) ");"))
- (wt-nl "base[0]=" (case return-type
- (fixnum (if (zerop *space*)
- "CMPmake_fixnum"
- "make_fixnum"))
- (character "code_char")
- (long-float "make_longfloat")
- (short-float "make_shortfloat")
- (otherwise ""))
- "(LI" cfun "(")
- (do ((types arg-types (cdr types))
- (n 0 (1+ n)))
- ((endp types))
- (declare (object types) (fixnum n))
- (wt (case (car types)
- (fixnum "fix")
- (character "char_code")
- (long-float "lf")
- (short-float "sf")
- (otherwise ""))
- "(base[" n "])")
- (unless (endp (cdr types)) (wt ",")))
- (wt "));")
- (wt-nl "vs_top=(vs_base=base)+1;")
- (wt-nl1 "}")
- )
-
- (defun rep-type (type)
- (case type
- (fixnum "int ")
- (character "unsigned char ")
- (short-float "float ")
- (long-float "double ")
- (otherwise "object ")))
-
-
- (defun t1defmacro (args)
- (when (or (endp args) (endp (cdr args)))
- (too-few-args 'defmacro 2 (length args)))
- (cmpck (not (symbolp (car args)))
- "The macro name ~s is not a symbol." (car args))
- (when *compile-time-too* (cmp-eval (cons 'defmacro args)))
- (setq *non-package-operation* t)
- (let ((*vars* nil) (*funs* nil) (*blocks* nil) (*tags* nil)
- (*sharp-commas* nil) (*special-binding* nil)
- macro-lambda (cfun (next-cfun)) (doc nil) (ppn nil))
- (setq macro-lambda (c1dm (car args) (cadr args) (cddr args)))
- (when (car macro-lambda) (setq doc (add-object (car macro-lambda))))
- (when (cadr macro-lambda) (setq ppn (add-object (cadr macro-lambda))))
- (add-load-time-sharp-comma)
- (push (list 'defmacro (car args) cfun (cddr macro-lambda) doc ppn
- *special-binding*)
- *top-level-forms*))
- )
-
- (defun t2defmacro (fname cfun macro-lambda doc ppn sp
- &aux (vv (add-symbol fname)))
- (declare (ignore macro-lambda sp))
- (when doc
- (wt-nl "(void)putprop(VV[" vv "],VV[" doc "],siSfunction_documentation);")
- (wt-nl) (reset-top))
- (when ppn
- (wt-nl "(void)putprop(VV[" vv "],VV[" ppn "],siSpretty_print_format);")
- (wt-nl) (reset-top))
- (wt-h "static L" cfun "();")
- (wt-nl "MM(VV[" vv "],L" cfun ",start,size,data);")
- )
-
- (defun t3defmacro (fname cfun macro-lambda doc ppn sp
- &aux (*vs* 0) (*max-vs* 0)
- (*clink* nil) (*ccb-vs* 0) (*level* 0)
- (*exit* 'return) (*unwind-exit* '(return))
- (*value-to-go* 'return)
- (*reservation-cmacro* (next-cmacro)))
- (declare (ignore doc ppn))
- (wt-comment "macro definition for " fname)
- (wt-nl1 "static L" cfun "()")
- (wt-nl1 "{ register object *base=vs_base;")
- (wt-nl "register object *sup=base+VM" *reservation-cmacro* ";")
- (if *safe-compile*
- (wt-nl "vs_reserve(VM" *reservation-cmacro* ");")
- (wt-nl "vs_check;"))
- (when sp (wt-nl "bds_check;"))
- (when *compiler-push-events* (wt-nl "ihs_check;"))
- (c2dm (car macro-lambda) (cadr macro-lambda) (caddr macro-lambda)
- (cadddr macro-lambda))
- (wt-nl1 "}")
- (push (cons *reservation-cmacro* *max-vs*) *reservations*)
- )
-
- (defun t1ordinary (form)
- (when *compile-time-too* (cmp-eval form))
- (setq *non-package-operation* t)
- (let ((*vars* nil) (*funs* nil) (*blocks* nil) (*tags* nil)
- (*sharp-commas* nil))
- (setq form (c1expr form))
- (add-load-time-sharp-comma)
- (push (list 'ordinary (next-cfun) form) *top-level-forms*)))
-
- (defun t2ordinary (cfun form)
- (declare (ignore cfun))
- (let* ((*exit* (next-label)) (*unwind-exit* (list *exit*))
- (*value-to-go* 'trash))
- (c2expr form)
- (wt-label *exit*)))
-
- (defun add-load-time-sharp-comma ()
- (dolist* (vv (reverse *sharp-commas*))
- (push (list 'sharp-comma vv) *top-level-forms*)))
-
- (defun t2sharp-comma (vv)
- (wt-nl "data->v.v_self[" vv "]=VV[" vv "]=string_to_object(VV[" vv "]);")
- (wt-nl) (reset-top))
-
- (defun t2declare (vv)
- (wt-nl "VV[" vv "]->s.s_stype=(short)stp_special;"))
-
- (defun t1defvar (args &aux form (doc nil))
- (when *compile-time-too* (cmp-eval `(defvar ,@args)))
- (setq *non-package-operation* nil)
- (cond ((endp (cdr args))
- (push (list 'declare (add-symbol (car args))) *top-level-forms*))
- (t
- (unless (endp (cddr args)) (setq doc (add-object (caddr args))))
- (let* ((*vars* nil) (*funs* nil) (*blocks* nil) (*tags* nil)
- (*sharp-commas* nil))
- (setq form (c1expr (cadr args)))
- (add-load-time-sharp-comma))
- (push (list 'defvar (add-symbol (car args)) form doc)
- *top-level-forms*)))
- )
-
- (defun t2defvar (vv form doc)
- (wt-nl "VV[" vv "]->s.s_stype=(short)stp_special;")
- (let* ((*exit* (next-label)) (*unwind-exit* (list *exit*))
- (*value-to-go* (list 'DBIND vv)))
- (wt-nl "if(VV[" vv "]->s.s_dbind == OBJNULL){")
- (c2expr form)
- (wt "}")
- (wt-label *exit*))
- (when doc
- (wt-nl "(void)putprop(VV[" vv "],VV[" doc "],siSvariable_documentation);")
- (wt-nl) (reset-top)
- )
- )
-
- (si:putprop 'dbind 'set-dbind 'set-loc)
-
- (defun set-dbind (loc vv)
- (wt-nl "VV[" vv "]->s.s_dbind = " loc ";"))
-
- (defun t1clines (args)
- (dolist** (s args)
- (cmpck (not (stringp s)) "The argument to CLINE, ~s, is not a string." s))
- (push (list 'clines args) *top-level-forms*))
-
- (defun t3clines (ss) (dolist** (s ss) (wt-nl1 s)))
-
- (defun t1defcfun (args &aux (body nil))
- (when (or (endp args) (endp (cdr args)))
- (too-few-args 'defcfun 2 (length args)))
- (cmpck (not (stringp (car args)))
- "The first argument to defCfun ~s is not a string." (car args))
- (cmpck (not (numberp (cadr args)))
- "The second argument to defCfun ~s is not a number." (cadr args))
- (dolist** (s (cddr args))
- (cond ((stringp s) (push s body))
- ((consp s)
- (cond ((symbolp (car s))
- (cmpck (special-form-p (car s))
- "Special form ~s is not allowed in defCfun." (car s))
- (push (list (cons (car s) (parse-cvspecs (cdr s)))) body))
- ((and (consp (car s)) (symbolp (caar s))
- (not (if (eq (caar s) 'quote)
- (or (endp (cdar s))
- (not (endp (cddar s)))
- (endp (cdr s))
- (not (endp (cddr s))))
- (special-form-p (caar s)))))
- (push (cons (cons (caar s)
- (if (eq (caar s) 'quote)
- (list (add-object (cadar s)))
- (parse-cvspecs (cdar s))))
- (parse-cvspecs (cdr s)))
- body))
- (t (cmperr "The defCfun body ~s is illegal." s))))
- (t (cmperr "The defCfun body ~s is illegal." s))))
- (push (list 'defcfun (car args) (cadr args) (reverse body))
- *top-level-forms*)
- )
-
- (defun t3defcfun (header vs-size body &aux fd)
- (wt-comment "C function defined by " 'defcfun)
- (wt-nl1 header)
- (wt-nl1 "{")
- (wt-nl1 "object *vs=vs_top;")
- (wt-nl1 "object *old_top=vs_top+" vs-size ";")
- (when (> vs-size 0) (wt-nl "vs_top=old_top;"))
- (wt-nl1 "{")
- (dolist** (s body)
- (cond ((stringp s) (wt-nl1 s))
- ((eq (caar s) 'quote)
- (wt-nl1 (cadadr s))
- (case (caadr s)
- (object (wt "=VV[" (cadar s) "];"))
- (otherwise
- (wt "=object_to_" (string-downcase (symbol-name (caadr s)))
- "(VV[" (cadar s) "]);"))))
- (t (wt-nl1 "{vs_base=vs_top=old_top;")
- (dolist** (arg (cdar s))
- (wt-nl1 "vs_push(")
- (case (car arg)
- (object (wt (cadr arg)))
- (char (wt "code_char((int)" (cadr arg) ")"))
- (int (when (zerop *space*) (wt "CMP"))
- (wt "make_fixnum((int)" (cadr arg) ")"))
- (float (wt "make_shortfloat((double)" (cadr arg) ")"))
- (double (wt "make_longfloat((double)" (cadr arg) ")")))
- (wt ");"))
- (cond ((setq fd (assoc (caar s) *global-funs*))
- (cond (*compiler-push-events*
- (wt-nl1 "ihs_push(VV[" (add-symbol (caar s)) "]);")
- (wt-nl1 "L" (cdr fd) "();")
- (wt-nl1 "ihs_pop();"))
- (t (wt-nl1 "L" (cdr fd) "();"))))
- (*compiler-push-events*
- (wt-nl1 "super_funcall(VV[" (add-symbol (caar s)) "]);"))
- (*safe-compile*
- (wt-nl1 "super_funcall_no_event(VV[" (add-symbol (caar s))
- "]);"))
- (t (wt-nl1 "CMPfuncall(VV[" (add-symbol (caar s))
- "]->s.s_gfdef);"))
- )
- (unless (endp (cdr s))
- (wt-nl1 (cadadr s))
- (case (caadr s)
- (object (wt "=vs_base[0];"))
- (otherwise (wt "=object_to_"
- (string-downcase (symbol-name (caadr s)))
- "(vs_base[0]);")))
- (dolist** (dest (cddr s))
- (wt-nl1 "vs_base++;")
- (wt-nl1 (cadr dest))
- (case (car dest)
- (object
- (wt "=(vs_base<vs_top?vs_base[0]:Cnil);"))
- (otherwise
- (wt "=object_to_"
- (string-downcase (symbol-name (car dest)))
- "((vs_base<vs_top?vs_base[0]:Cnil));"))))
- )
- (wt-nl1 "}")
- )))
- (wt-nl1 "}")
- (wt-nl1 "vs_top=vs;")
- (wt-nl1 "}")
- )
-
- (defun t1defentry (args &aux type cname (cfun (next-cfun)) cfspec)
- (when (or (endp args) (endp (cdr args)) (endp (cddr args)))
- (too-few-args 'defentry 3 (length args)))
- (cmpck (not (symbolp (car args)))
- "The function name ~s is not a symbol." (car args))
- (dolist** (x (cadr args))
- (cmpck (not (member x '(object char int float double)))
- "The C-type ~s is illegal." x))
- (setq cfspec (caddr args))
- (cond ((symbolp cfspec)
- (setq type 'object)
- (setq cname (string-downcase (symbol-name cfspec))))
- ((stringp cfspec)
- (setq type 'object)
- (setq cname cfspec))
- ((and (consp cfspec)
- (member (car cfspec) '(void object char int float double))
- (consp (cdr cfspec))
- (or (symbolp (cadr cfspec)) (stringp (cadr cfspec)))
- (endp (cddr cfspec)))
- (setq cname (if (symbolp (cadr cfspec))
- (string-downcase (symbol-name (cadr cfspec)))
- (cadr cfspec)))
- (setq type (car cfspec)))
- (t (cmperr "The C function specification ~s is illegal." cfspec)))
- (push (list 'defentry (car args) cfun (cadr args) type cname)
- *top-level-forms*)
- (push (cons (car args) cfun) *global-funs*)
- )
-
- (defun t2defentry (fname cfun arg-types type cname
- &aux (vv (add-symbol fname)))
- (declare (ignore arg-types type cname))
- (wt-h "static L" cfun "();")
- (wt-nl "MF(VV[" vv "],L" cfun ",start,size,data);")
- )
-
- (defun t3defentry (fname cfun arg-types type cname)
- (wt-comment "function definition for " fname)
- (wt-nl1 "static L" cfun "()")
- (wt-nl1 "{ object *old_base=vs_base;")
- (unless (eq type 'void) (wt-nl (string-downcase (symbol-name type)) " x;"))
- (when *safe-compile* (wt-nl "check_arg(" (length arg-types) ");"))
- (unless (eq type 'void) (wt-nl "x="))
- (wt-nl cname "(")
- (unless (endp arg-types)
- (do ((types arg-types (cdr types))
- (i 0 (1+ i)))
- (nil)
- (declare (object types) (fixnum i))
- (case (car types)
- (object (wt-nl "vs_base[" i "]"))
- (otherwise
- (wt-nl "object_to_"
- (string-downcase (symbol-name (car types)))
- "(vs_base[" i "])")))
- (when (endp (cdr types)) (return))
- (wt ",")))
- (wt ");")
- (wt-nl "vs_top=(vs_base=old_base)+1;")
- (wt-nl "vs_base[0]=")
- (case type
- (void (wt "Cnil"))
- (object (wt "x"))
- (char (wt "code_char(x)"))
- (int (when (zerop *space*) (wt "CMP"))
- (wt "make_fixnum(x)"))
- (float (wt "make_shortfloat(x)"))
- (double (wt "make_longfloat(x)"))
- )
- (wt ";")
- (wt-nl1 "}")
- )
-
- (defun t1defla (args) (declare (ignore args)))
-
- (defun parse-cvspecs (x &aux (cvspecs nil))
- (dolist** (cvs x (reverse cvspecs))
- (cond ((symbolp cvs)
- (push (list 'object (string-downcase (symbol-name cvs))) cvspecs))
- ((stringp cvs) (push (list 'object cvs) cvspecs))
- ((and (consp cvs)
- (member (car cvs) '(object char int float double)))
- (dolist** (name (cdr cvs))
- (push (list (car cvs)
- (cond ((symbolp name)
- (string-downcase (symbol-name name)))
- ((stringp name) name)
- (t (cmperr "The C variable name ~s is illegal."
- name))))
- cvspecs)))
- (t (cmperr "The C variable specification ~s is illegal." cvs))))
- )
-
- (defun t3local-fun (closure-p clink ccb-vs fun lambda-expr
- &aux (level (if closure-p 0 (fun-level fun))))
- (declare (fixnum level))
- (wt-comment "local function " (if (fun-name fun) (fun-name fun) nil))
- (wt-nl1 "static " (if closure-p "LC" "L") (fun-cfun fun) "(")
- (dotimes* (n level (wt "base" n ")")) (wt "base" n ","))
- (wt-nl1 "register object ")
- (dotimes* (n level (wt "*base" n ";")) (wt "*base" n ","))
- (let ((*vs* 0) (*max-vs* 0) (*clink* clink) (*ccb-vs* ccb-vs)
- (*level* (1+ level)) (*initial-ccb-vs* ccb-vs)
- (*exit* 'return) (*unwind-exit* '(return))
- (*value-to-go* 'return) (*reservation-cmacro* (next-cmacro)))
- (wt-nl1 "{ register object *base=vs_base;")
- (wt-nl "register object *sup=base+VM" *reservation-cmacro* ";")
- (if *safe-compile*
- (wt-nl "vs_reserve(VM" *reservation-cmacro* ");")
- (wt-nl "vs_check;"))
- (when *compiler-push-events* (wt-nl "ihs_check;"))
- (if closure-p
- (c2lambda-expr (caddr lambda-expr) (caddr (cddr lambda-expr)))
- (c2lambda-expr (caddr lambda-expr) (caddr (cddr lambda-expr)) fun))
- (wt-nl1 "}")
- (push (cons *reservation-cmacro* *max-vs*) *reservations*))
- )
-